home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
smaltalk
/
manchest.lha
/
MANCHESTER
/
manchester
/
4.1
/
calculator.st
< prev
next >
Wrap
Text File
|
1993-07-24
|
22KB
|
794 lines
" NAME calculator
AUTHOR various (see summary)
FUNCTION A simple four-function calculator
ST-VERSION 4.1
PREREQUISITES
CONFLICTS
DISTRIBUTION world
VERSION 1
DATE 24 Nov 1992
SUMMARY
This is a simple four-function calculator.
The original for 2.X, was by Trevor Hopkins (tph@cs.man.ac.uk). it
was subsequently ported to R4 by Bernard Horan
(bernard@com.morgan.is). A few minor mods were made by Mario Wolczko
(mario@cs.man.ac.uk). Somewhere along the line the class comments
were lost.
While the 2.X version was a good example of view construction, this
may not be such an examplar for R4...
"
'From Objectworks\Smalltalk(R), Release 4.1 of 15 April 1992 on 24 November 1992 at 1:14:54 pm'!
DialogView subclass: #KeypadView
instanceVariableNames: ''
classVariableNames: 'KeyComponents TextStyle '
poolDictionaries: ''
category: 'Calculator'!
!KeypadView methodsFor: 'accessing'!
defaultController
^KeypadViewController new!
dispatchesKeyboard
^true!
model: aCalculator
super model: aCalculator.
self buildSubViews!
subViewContainingCharacter: aCharacter
"Answer the receiver's subView that corresponds to the key,
aCharacter.
Answer nil if no subView is selected by aCharacter."
"This is an atrocious hack, and is based on a the way the views are created
(see private method). This is because I am a subclass of DialogView. The long
concatenated unary messages pluck out my wrappers (on ButtonViews)"
self components first component components reverseDo: [:aWrapper |
(aWrapper component containsKey: aCharacter asLowercase)
ifTrue: [^aWrapper component]].
^nil! !
!KeypadView methodsFor: 'private'!
buildSubViews
"Build my buttons"
"If you change this you may have to change the method #subViewContainingCharacter.
The order of the elements has to match the order of the characters, and gives the order of the buttons on the display"
| elements chars |
elements := #(#add7 #add8 #add9 #clearEntry #clear #add4 #add5 #add6 #multiply #divide #add1 #add2 #add3 #add #subtract #add0 #point #raiseTo #changeSign #equals ).
chars := #($7 $8 $9 $e $c
$4 $5 $6 $* $/
$1 $2 $3 $+ $-
$0 $. $^ $s $=).
self
addAll: (1 to: elements size)
inRows: 4
fromX: 0
toX: 1
collect:
[:i |
| button view wrapper element|
element := elements at: i.
button := (PluggableAdaptor on: model)
getBlock: [:m | false]
putBlock: [:m :a | m perform: element]
updateBlock: [:m :a :p | false].
view := ButtonView model: button.
view beVisual: (KeyComponents at: element).
view key: (chars at: i).
view controller beTriggerOnUp.
wrapper := BorderedWrapper on: view.
wrapper insideColor: ColorValue white.
wrapper]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
KeypadView class
instanceVariableNames: ''!
!KeypadView class methodsFor: 'class initialization'!
initialize
"KeypadView initialize."
self initializeTextStyle.
self initializeKeyComponents!
initializeKeyComponents
"KeypadView initializeKeyComponents."
"A Dictionary of VisualComponents to be used for the buttons"
| pixmap image |
KeyComponents := Dictionary new.
0 to: 9 do: [:number | KeyComponents at: ('add' , number printString) asSymbol put: (ComposedText withText: number printString asText style: self textStyle)].
pixmap := Pixmap extent: 15 @ 15.
pixmap graphicsContext
displayWedgeBoundedBy: (pixmap bounds insetBy: 3 @ 3)
startAngle: 0
sweepAngle: 360.
KeyComponents at: #clearEntry put: pixmap asImage.
KeyComponents at: #equals put: (ComposedText withText: '=' asText style: self textStyle).
KeyComponents at: #add put: (ComposedText withText: '+' asText style: self textStyle).
KeyComponents at: #subtract put: (ComposedText withText: '-' asText style: self textStyle).
KeyComponents at: #multiply put: (ComposedText withText: 'X' asText style: self textStyle).
KeyComponents at: #divide put: (ComposedText withText: '/' asText style: self textStyle).
image := Image
extent: 10 @ 14
depth: 1
palette: MappedPalette whiteBlack
words: #(12288 12288 64512 64704 12672 13056 1536 3072 6144 12288 26560 51136 0 0 ).
KeyComponents at: #changeSign put: image.
image := Image
extent: 10 @ 14
depth: 1
palette: MappedPalette whiteBlack
words: #(0 1088 1088 640 256 256 512 35328 34816 20480 8192 20480 34816 34816 ).
KeyComponents at: #raiseTo put: image.
KeyComponents at: #point put: (ComposedText withText: '.' asText style: self textStyle).
KeyComponents at: #clear put: (ComposedText withText: 'C' asText style: self textStyle)!
initializeTextStyle
"The textStyle used when creating (some of) the buttons. See method #initializeKeyComponents"
TextStyle := (TextAttributes defaultFontQuery: ((FontDescription new) fixedWidth: false; serif: false; italic: false; boldness: 0.5; pixelSize: 18))
lineGrid: 20;
baseline: 15! !
!KeypadView class methodsFor: 'private'!
textStyle
^TextStyle! !
Model subclass: #Calculator
instanceVariableNames: 'displayValue accumulatorValue currentOperation doneOperation noOfDigits errorFlag pointPlaces trailingZeros leftJustify '
classVariableNames: 'DefaultNoOfDigits '
poolDictionaries: ''
category: 'Calculator'!
!Calculator methodsFor: 'initialize-release'!
initialize
"Initialize the receiver."
displayValue := 0.
accumulatorValue := 0.
currentOperation := nil.
doneOperation := true.
errorFlag := false.
pointPlaces := 0.
trailingZeros := 0.
leftJustify := true.
noOfDigits := DefaultNoOfDigits! !
!Calculator methodsFor: 'accessing'!
displayValue
"Answers with the current display value."
^displayValue!
errorFlag
"Answer the error flag value."
^errorFlag!
leftJustify
"Answer the current value of the left justify flag."
^leftJustify!
leftJustify: aBoolean
"Set the current value of the left justify flag."
leftJustify := aBoolean.
self changed!
noOfDigits
"Answer the number of digits represented."
^noOfDigits!
noOfDigits: aNumber
"Sets the number of digits represented to aNumber."
noOfDigits := aNumber.
self changed!
pointPlaces
^pointPlaces!
trailingZeros
"Answer the number of trailing zeros."
^trailingZeros! !
!Calculator methodsFor: 'operation keys'!
add
"Make the current operation addition."
self doOperation.
currentOperation := #addition.!
changeSign
"Change the sign of the value in the display register."
self makeDisplay: displayValue negated!
clear
"Clear the error flag. Clear the display and accumulator registers."
errorFlag := false.
pointPlaces := 0.
trailingZeros := 0.
accumulatorValue := 0.
currentOperation := nil.
self makeDisplay: 0!
clearEntry
"Zero the display register."
pointPlaces := 0.
trailingZeros := 0.
self makeDisplay: 0!
divide
"Make the current operation division."
self doOperation.
currentOperation := #division!
equals
"Perform the current operation, putting the answer in
the accumulator. Display the answer."
self performOperation: currentOperation.
self makeDisplay: accumulatorValue.
doneOperation := true.
trailingZeros := 0.
currentOperation := nil!
multiply
"Make the current operation multiplication."
self doOperation.
currentOperation := #multiplication!
point
"Insert a decimal point. Sets the number of decimal places to 1."
pointPlaces = 0 ifTrue: [pointPlaces := 1]!
raiseTo
"Make the current operation raise-to-power."
self doOperation.
currentOperation := #raiseTo!
subtract
"Make the current operation subtraction."
self doOperation.
currentOperation := #subtraction.! !
!Calculator methodsFor: 'digit keys'!
add0
"Add 0 to the display value."
pointPlaces > 0 ifTrue: [trailingZeros := trailingZeros + 1].
self addToDisplay: 0.!
add1
"Add 1 to the display value."
trailingZeros := 0.
self addToDisplay: 1.!
add2
"Add 2 to the display value."
trailingZeros := 0.
self addToDisplay: 2.!
add3
"Add 3 to the display value."
trailingZeros := 0.
self addToDisplay: 3.!
add4
"Add 4 to the display value."
trailingZeros := 0.
self addToDisplay: 4.!
add5
"Add 5 to the display value."
trailingZeros := 0.
self addToDisplay: 5.!
add6
"Add 6 to the display value."
trailingZeros := 0.
self addToDisplay: 6.!
add7
"Add 7 to the display value."
trailingZeros := 0.
self addToDisplay: 7.!
add8
"Add 8 to the display value."
trailingZeros := 0.
self addToDisplay: 8.!
add9
"Add 9 to the display value."
trailingZeros := 0.
self addToDisplay: 9.! !
!Calculator methodsFor: 'private'!
addToDisplay: aNumber
"Adds a number to the display value. The model has
changed."
| temp |
doneOperation ifTrue: [
displayValue := 0.
doneOperation := false].
displayValue < 0
ifTrue: [temp := aNumber negated]
ifFalse: [temp := aNumber].
pointPlaces ~= 0
ifTrue: [
self makeDisplay: displayValue +
(temp / (10 raisedToInteger: pointPlaces)).
pointPlaces := pointPlaces + 1]
ifFalse: [self makeDisplay: displayValue * 10 + temp]!
doOperation
"Do the current operation (if any). Update the display
and accumulator."
currentOperation notNil ifTrue: [
self performOperation: currentOperation.
self makeDisplay: accumulatorValue].
trailingZeros := 0.
pointPlaces := 0.
doneOperation := true.
accumulatorValue := displayValue.!
makeDisplay: aNumber
"Makes aNumber the display value. The model has changed."
aNumber >= (10 raisedToInteger: noOfDigits)
ifTrue: [errorFlag := true]
ifFalse: [displayValue := aNumber].
self changed!
performOperation: aSymbol
"Perform the operation given by aSymbol."
aSymbol = #addition ifTrue: [
accumulatorValue := accumulatorValue + displayValue].
aSymbol = #subtraction ifTrue: [
accumulatorValue := accumulatorValue - displayValue].
aSymbol = #multiplication ifTrue: [
accumulatorValue := accumulatorValue * displayValue].
aSymbol = #division ifTrue: [
displayValue = 0
ifTrue: [errorFlag := true.]
ifFalse: [accumulatorValue := accumulatorValue / displayValue]].
aSymbol = #raiseTo ifTrue: [
accumulatorValue := accumulatorValue raisedTo: displayValue].
pointPlaces := 0! !
!Calculator methodsFor: 'views'!
openCalculatorView
"Calculator new openCalculatorView"
| keypadView window digitView comp extent |
extent := 230 @ 150.
keypadView := KeypadView model: self.
digitView := DigitView model: self.
comp := CompositePart new.
comp add: digitView borderedIn:
(LayoutFrame
leftFraction: 0 offset: 0 rightFraction: 1 offset: 0
topFraction: 0 offset: 0 bottomFraction: 0 offset: 40).
comp add: keypadView borderedIn:
(LayoutFrame
leftFraction: 0 offset: 0 rightFraction: 1 offset: 0
topFraction: 0 offset: 40 bottomFraction: 1 offset: 0).
window := ScheduledWindow new.
window label: 'Calculator'.
window component: comp.
window minimumSize: extent.
window open!
openDigitView
"Calculator new openDigitView"
| digitView window wrapper |
digitView := DigitView model: self.
window := ScheduledWindow new.
window label: 'Digits'.
wrapper := BorderedWrapper on: digitView.
wrapper insideColor: ColorValue white.
window component: wrapper.
window open!
openKeypadView
"Calculator new openKeypadView"
| keypadView window |
keypadView := KeypadView model: self.
window := ScheduledWindow new.
window label: 'Keypad'.
window component: keypadView.
window open! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Calculator class
instanceVariableNames: ''!
!Calculator class methodsFor: 'instance creation'!
new
"Create a new initialized instance of the receiver."
^super new initialize!
new: aNumber
"Create a new instance of the receiver, with aNumber digits."
^self new noOfDigits: aNumber!
openView
"Calculator openView"
Calculator new openCalculatorView! !
!Calculator class methodsFor: 'class initialization'!
initialize
"Initialize default values."
"Calculator initialize."
DefaultNoOfDigits := 12! !
!Image class methodsFor: 'instance creation'!
extent: extentPoint depth: depth palette: palette words: aWordArray
"Answer an Image with the specified extent, palette, and bitmap contents.
The bitmap contents should be specified by a WordArray in the standard
bitmap format: Z pixel format (contiguous pixel bits), MS byte order and bit
order, scanline padding to a multiple of 32 bits, and bitsPerPixel either 1,
2, 4, 8, or 24. The bitsPerPixel should be the lowest supported value >= depth."
| aByteArray |
aByteArray := ByteArray new: aWordArray size * 2.
1 to: aWordArray size do: [:i |
aByteArray at: i * 2 put: ((aWordArray at: i) bitAnd: 255).
aByteArray at: i * 2 - 1 put: ((aWordArray at: i) bitShift: -8)].
^self extent: extentPoint depth: depth palette: palette bits: aByteArray pad: 16! !
LabeledBooleanView subclass: #ButtonView
instanceVariableNames: 'key '
classVariableNames: ''
poolDictionaries: ''
category: 'Calculator'!
!ButtonView methodsFor: 'accessing'!
containsKey: aChar
"Test to see if aChar is the same as mine own"
^key = aChar!
key: aChar
"Set my char"
key := aChar!
sendMessage
"I've been 'pressed' "
model value: true! !
View subclass: #DigitView
instanceVariableNames: 'sevenSegImages cachedImageSize '
classVariableNames: ''
poolDictionaries: ''
category: 'Calculator'!
!DigitView methodsFor: 'initialize-release'!
initialize
super initialize.
sevenSegImages := Array new: 12.! !
!DigitView methodsFor: 'displaying'!
displayErrorOn: aGraphicsContext
"Display the error indication - a letter E."
((sevenSegImages at: 12) notNil and: [cachedImageSize = self currentImageSize])
ifFalse: [self newCachedImages].
(sevenSegImages at: 12) displayOn: aGraphicsContext at: self digitDisplayOrigin!
displayLeftDigits: aCollection on: aGraphicsContext
"Display, in seven segment form, the digits in aCollection,
starting from the left."
"The first field in the array is the right (least significant) digit."
| origin width |
((sevenSegImages at: 1) isNil or: [cachedImageSize ~= self currentImageSize])
ifTrue: [self newCachedImages].
width := self digitBox width.
origin := self digitDisplayOrigin.
1 to: aCollection size do: [ :count |
(sevenSegImages at: (aCollection at: count) truncated + 1)
displayOn: aGraphicsContext at: origin + (count * width@0) ]!
displayLeftPoint: aPosition on: aGraphicsContext
"Display a small black image representing the decimal point,
in a left justified manner."
| origin width size |
width := self digitBox width.
size := width // 8 max: 2.
origin := self bounds origin +
(width * aPosition@0) +
((size negated // 2)@(self formBox height + self digitOffset y - size)).
self point displayOn: aGraphicsContext at: origin!
displayMinusOn: aGraphicsContext
"Display the minus sign."
((sevenSegImages at: 11) notNil
and: [cachedImageSize = self currentImageSize])
ifFalse: [self newCachedImages].
(sevenSegImages at: 11) displayOn: aGraphicsContext at: self digitDisplayOrigin!
displayOn: aGraphicsContext
"Display the displayValue in seven-segment form."
| digits value remainder count noOfDigits pointPosition trailingZeros |
model errorFlag ifTrue: [^self displayErrorOn: aGraphicsContext].
value := model displayValue.
value < 0 ifTrue: [
self displayMinusOn: aGraphicsContext.
value := value negated].
noOfDigits := model noOfDigits.
digits := OrderedCollection new: noOfDigits.
count := 1.
remainder := value - value truncated.
[value >= 10] whileTrue: [
digits addFirst: value \\ 10.
value := value // 10.
count := count + 1].
digits addFirst: value truncated.
count := count + 1.
pointPosition := count.
[(count <= noOfDigits) & (remainder ~= 0)] whileTrue: [
remainder := remainder * 10.
value := remainder truncated.
digits addLast: value.
remainder := remainder - value.
count := count + 1].
trailingZeros := model trailingZeros.
[(count <= noOfDigits) & (trailingZeros > 0)] whileTrue: [
digits addLast: 0.
trailingZeros := trailingZeros - 1.
count := count + 1].
model leftJustify
ifTrue: [
self displayLeftDigits: digits on: aGraphicsContext.
self displayLeftPoint: pointPosition on: aGraphicsContext]
ifFalse: [
self displayRightDigits: digits on: aGraphicsContext.
self displayRightPoint: (count - pointPosition) on: aGraphicsContext].!
displayRightDigits: aCollection on: aGraphicsContext
"Display, in seven segment form, the digits in aCollection,
starting from the right hand side."
"The first field in the array is the right (least significant) digit."
| origin width noOfDigits |
width := self digitBox width.
origin := self digitDisplayOrigin.
((sevenSegImages at: 1) isNil or: [cachedImageSize ~= self currentImageSize])
ifTrue: [self newCachedImages].
noOfDigits := model noOfDigits + 1.
aCollection size to: 1 by: -1 do: [:count |
(sevenSegImages at: (aCollection at: aCollection size - count + 1) truncated + 1)
displayOn: aGraphicsContext at: origin + (noOfDigits - count * width @ 0)]!
displayRightPoint: aPosition on: aGraphicsContext
"Display a small black form representing the decimal point,
suitable for a right justified display."
| origin width size position |
position := model noOfDigits + 1 - aPosition.
width := self digitBox width.
size := width // 8 max: 2.
origin := self bounds origin + (width * position @ 0) + (size negated // 2 @ (self formBox height + self digitOffset y - size)).
self point displayOn: aGraphicsContext at: origin!
update: aParameter
self invalidate! !
!DigitView methodsFor: 'private'!
currentImageSize
"Answer with the new current image size."
^self formBox extent!
defaultControllerClass
^DigitController!
digitBox
"Answers a rectangle which is the box used to divide up
the calculator digit display area."
| box |
box := self bounds copy.
box width: (box width // (model noOfDigits +1)).
^box!
digitDisplayOrigin
"Answer the origin for a digit display form for display."
^(self bounds origin) + (self digitOffset)!
digitOffset
"Offset between digitBox and formBox."
^(self formBox origin) - (self digitBox origin)!
formBox
"Answers a rectangle which is the box used to display the
calculator digits."
| box |
box := self digitBox.
^box insetBy: (box width // 8 max: 3)@(box height // 8 max: 3)!
newCachedImages
"Re-calculates all the cached images."
| size halfHeight lineWidth |
size := self currentImageSize.
lineWidth := (size x / 8 max: 2)
roundTo: 2.
halfHeight := size y / 2 + (lineWidth / 2).
0 to: 11 do:
[:count |
| mask gc |
mask := Mask extent: size.
gc := mask graphicsContext.
(#(1 3 4 5 7 9 10 ) includes: count)
ifFalse: ["Bottom Left Segment."
gc displayRectangle: (0 @ (size y - halfHeight + 1) extent: lineWidth @ halfHeight)].
(#(2 10 11 ) includes: count)
ifFalse: ["Bottom Right Segment."
gc displayRectangle: (size x - lineWidth @ (size y - halfHeight + 1) extent: lineWidth @ halfHeight)].
(#(1 4 7 10 ) includes: count)
ifFalse: ["Bottom Segment."
gc displayRectangle: (0 @ (size y - lineWidth) extent: size x @ lineWidth)].
(#(0 1 7 ) includes: count)
ifFalse: ["Center Segment."
gc displayRectangle: (0 @ (size y - halfHeight) extent: size x @ lineWidth)].
(#(1 2 3 7 10 ) includes: count)
ifFalse: ["Top Left Segment."
gc displayRectangle: (0 @ 0 extent: lineWidth @ halfHeight)].
(#(5 6 10 11 ) includes: count)
ifFalse: ["Top Right Segment."
gc displayRectangle: (size x - lineWidth @ 0 extent: lineWidth @ halfHeight)].
(#(1 4 10 ) includes: count)
ifFalse: ["Top Segment."
gc displayRectangle: (0 @ 0 extent: size x @ lineWidth)].
sevenSegImages at: count + 1 put: mask].
cachedImageSize := size!
point
| width size |
width := self digitBox width.
size := width // 8 max: 2.
^Image
extent: size @ size
depth: 1
palette: MappedPalette blackWhite! !
ControllerWithMenu subclass: #DigitController
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Calculator'!
!DigitController methodsFor: 'menu messages'!
changeDigitLength
"Change the number of digits displayed."
| answerString |
answerString := DialogView
request: 'Number of digits to be displayed?'
initialAnswer: model noOfDigits printString.
answerString isEmpty ifFalse: [
model noOfDigits: (Number readFrom: (ReadStream on: answerString))]!
setLeftJustify
"Display as left-justified."
model leftJustify ifFalse: [model leftJustify: true]!
setRightJustify
"Display as right-justified."
model leftJustify ifTrue: [model leftJustify: false]! !
!DigitController methodsFor: 'private'!
menu
^PopUpMenu
labels: ' Digit Length \ Left Justify \ Right Justify ' withCRs
lines: #(1)
values: #(changeDigitLength setLeftJustify setRightJustify).! !
Controller subclass: #KeypadViewController
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Calculator'!
!KeypadViewController methodsFor: 'control'!
viewWantingControl
"If the keyboard has been pressed, then deal with it. Otherwise return the object under the cursor"
(self isControlWanted and: [self sensor keyboardPressed])
ifTrue:
[self processKeyboard].
^view componentWantingControl! !
!KeypadViewController methodsFor: 'private'!
processKeyboard
"The user typed a key on the keyboard. Tell the appropriate button that it
is selected by this key."
|button |
button := view subViewContainingCharacter: sensor keyboard.
button notNil
ifTrue: [button sendMessage]
ifFalse: [Screen default ringBell]! !
Calculator initialize!
KeypadView initialize!